home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Magnum One
/
Magnum One (Mid-American Digital) (Disc Manufacturing).iso
/
d1
/
buffer.arc
/
SPOOL.ASM
< prev
next >
Wrap
Assembly Source File
|
1988-07-24
|
39KB
|
1,074 lines
page 64,132
;----------------------------------------------------------------------------
; spooler program
;
; modified by craig derouen 6-6-84
;
; Version 2.0 by craig derouen 3-20-85
; : change communications interrupt with buffer
; : control to ioctl for better,more compatable
; : operation. Change additional interrupt to user
; : modifiable in case of conflicts.
; Version 2.2 by Craig Derouen 4-4-85
; : Change status return code so more compat with
; : other programs. Add a pause feature. Add reprint
; : last page feature.
;
; Configuring spooler:
;
; Install the folowing line you CONFIG.SYS file on the boot
; disk:
; device=spool.dev [/option1] [/option2]
;
; Where option may be the following:
; Option 1: "/1" -"/64" Decimal digit(s) indicating
; (k)size of memory to reserve for print
; buffer.
;
; Option 2: "/L(1,2,3)" or "/C(1,2)". Specifies which
; port is buffered, and becomes STANDARD
; PRN output. Only one may be specified.
; Option "L(1,2,3)" indicates LPT1,LPT2 or
; LPT3 respectively. Option "/C(1,2)" indicates
; Com1 or Com2 port.
;
; Thus if the following line is installed:
;
; device = spool.dev /l2 /60
;
; It means spool the PRN output to LPT2, reserve a 60K buffer.
;
; Options are not case sensitive! Options may be installed in
; any order. Any other characters are ignored. Default setup
; is:
; LPT1 and 1K buffer
;
user_int equ 67h ; Required additional interrupt. Just change
; it here if conflicts with anything.
formfeed equ 0ch ; Form feed char. This is the char the code
; looks for to indicate new page
;----------------------------------------------------------------------------
cseg segment para public 'CODE'
assume cs:cseg,es:cseg,ds:cseg
;----------------------------------------------------------------------------
; device driver header
;----------------------------------------------------------------------------
next_dev dd -1 ;pointer to next device
attribute dw 0C000h ;character type device with ioctl
strategy dw dev_strategy ;pointer to device strategy
interrupt dw dev_int ;pointer to dev_int
dev_name db 'PRN ' ;device indentifier
;-----------------------------------------------------------------------------
; f u n c t i o n t a b l e
;
; this is the table of procedures which are called to service each type
; of device driver request from ms-dos.
;-----------------------------------------------------------------------------
funtab label byte
dw init ;initialization routine
dw exit ;media check (block only)
dw exit ;build bpb "" ""
dw ioctl_in ;ioctl input
dw exit ;input (read)
dw nd_input ;non_destructive input no wait (char only)
dw exit ;input status
dw exit ;input flush
dw output ;output (write)
dw output ;output (write) with verify
dw out_stat ;output status
dw out_flush ;output flush
dw ioctl_out ;ioctl output
;-----------------------------------------------------------------------------
; working variables for bufferring of output
;-----------------------------------------------------------------------------
port_type db 0 ;flag specifying lpt or com port - com=0, lpt=1
rh_seg dd 0 ;request header pointer - segment and offset
data_seg dw 0 ;data segment for printer data
ending_address dw 0 ; this is the value past back to dos from the initialization routine
pull_ptr dw 0 ;points to the current character to output from the buffer
insert_ptr dw 0 ;points place to insert next character into buffer
buf_size dw 0 ;size of the printer buffer in characters
port_number db 0 ;current port number of output port (0,1) if com, (0,1,2) if parallel
move_cnt dw 0 ;amount of data moved
buf_flg db 0 ;not zero if buffer full
buff_cnt dw 0 ;amount of data in the buffer
loop_cnt dw 0 ;number of times around the loop
priority dw 100 ;processing priority
pointer_set db 0 ;non-zero if irq0 vector modifyied
ppause db 0 ; flag for printer pause
;-----------------------------------------------------------------------------
; device strategy routine
;
; this procedure gets the request header from ms-dos and sets up rh_seg
; as the pointer used in the buffer driver for manipulation of the request
; header
; entry: ex:bx --> pointer to request header from ms-dos
;
; exit: rh_seg --> our internal pointer to request header
;-----------------------------------------------------------------------------
dev_strategy proc far
mov word ptr cs:[rh_seg],bx ;save the request header segment
mov word ptr cs:[rh_seg+2],es ;save the request header offset
ret
dev_strategy endp
;------------------------------------------------------------------------------
;
; device interrupt handler
;
; this procedure is called each time ms-dos calls the driver. its task
; is to branch control to the proper procedure to service the request.
;
; this procedure saves all registers, uses rh_seg (pointer to request
; header) to get the command number, then uses the command number as an offset
; into the command table (funtab) to jump to the appropriate procedure to service
; the request from ms-dos to the driver
;
; entry: rh_seg --> pointer to request header
;
; exit: cx --> number of bytes to transfer (read or write)
; ex:di --> pointer to data (transfer address)
; jump to proper procedure to service request, if valid, or
; jump to ioctl_in if invalid command
;-----------------------------------------------------------------------------
dev_int proc far
push si
mov si,offset funtab ;point to the start of the function table
push ax ;save all registers onto the stack
push bx
push cx
push dx
push di
push bp
push ds
push es
lds bx,cs:rh_seg ;get the request header segment
mov cx,[bx+12h] ;get the amount of data to transfer
mov al,[bx+02h] ;get the command byte
cbw ;make 16 bit value
add si,ax ;add into our table value
add si,ax ;do it again
cmp al,12 ;is it above the last entry in our table
ja exit ;do null action if so
les di,[bx]+14d ;get pointer to our data
push cs ;make our data segment register
pop ds ;the same as our code segment register
jmp word ptr[si] ;jump to correct action in the table
;-----------------------------------------------------------------------------
; non destructive input routine
;
; this procedure always returns done and busy to ms-dos to indicate that
; there is no character in the buffer to return.
;
; entry: rh_seg --> pointer to request header from ms-dos
;
; exit: rh_seg --> return request header with done and busy set in
; status word, no other changes are made to the request header
; ah --> 0011 (done and busy bits set)
;----------------------------------------------------------------------------
nd_input:
mov ah,03 ;indicate done and buzy to dos
jmp short exit1 ;set our status word
;----------------------------------------------------------------------------
; dummy return point
;
; this is the return procedure for exiting the driver and returning control
; to ms-dos. the status word can be updated to indicate done and number of
; characters processed. the registers which were previously saved are restored
; prior to exiting.
;
; entry: ax,cx --> ah and al can be previously set as the status word
; should be jmped to.
;
; exit: ds:bx --> pointer to update request header to return to ms-dos
; es,ds,bp,di,dx,cx,bx,ax,si restored in that order
;-----------------------------------------------------------------------------
exit: mov ah,01 ;indicate done for status word
mov cx,cs:move_cnt ;get the amount of data move
exit1: lds bx,cs:rh_seg ;load request header segment
mov [bx+03],ax ;save our exit status word
mov [bx+12h],cx ;save the amount of data read
pop es ;restore the entry registers from the
pop ds ;stack before exiting
pop bp
pop di
pop dx
pop cx
pop bx
pop ax
pop si
ret
dev_int endp
;-----------------------------------------------------------------------------
; output status routine
;
; this procedure returns status based on the amount of characters in the
; buffer. if the buffer is full (buff_cnt = buf_size) then a jmp to nd_input
; is done to return busy and done to ms-dos, otherwise a jmp to exit is done
; to return done.
;
; entry: buff_cnt, buf_size are compared to see if the buffer is full
;
; exit: a jump is performed based on the amount of characters in the
; buffer.
;-----------------------------------------------------------------------------
out_stat proc near
out_stat1:mov bx,buff_cnt ;get amount of characters in the buffer
cmp bx,buf_size ;is it the same as our total buffer space
jnz exit ;indicate done to dos
jmp nd_input ;indicate buzy and done to the operating system
out_stat endp
;------------------------------------------------------------------------------
; output routine
;
; this procedure services all write requests from ms-dos. this is done by
; inserting characters into the buffer until all characters have been inserted.
; each character is put into al and then insert is called which performs the
; insertion into the buffer. this is performed repeatedly until all characters
; have been transferred into the buffer.
;
; entry: cx --> number of characters to transfer into the buffer
; es:di --> pointer to data area of characters to transfer
;
; exit: move_cnt --> number of characters transferred into the buffer
;-----------------------------------------------------------------------------
output proc near
sti ;start interrupts just in case
output1:cld ;clear direction flag
mov move_cnt,0 ;set number of characters accepted to zero
output2:mov al,es:[di] ;get the character from requester
call insert ;insert the character into local buffer
inc move_cnt ;increment the amount of data moved
inc di ;bump the pointer to the next character
loop output2 ;loop untill all data inserted into the buffer
jmp exit ;set status word to done and exit
output endp
;-----------------------------------------------------------------------------
; insert character into printer buffer
;
; this procedure performs the task of inserting characters into the buffer.
; the procedure does an idle loop while the buffer is full because the buffer is
; being emptied in a background method. once there is room in the buffer, the
; insert_ptr is incremented to point to the next position. if it points past
; the end of the buffer, it is set to point to the front of the buffer (a
; circular queue). once the correct insert point is established, the character
; is written to memory and the buffer count is incremented to indicate the
; insertion of the character. interrupts are disabled for the short period
; when the character is actually written to memory and the buffer count is
; incremented.
;
; entry: al --> character to insert into the buffer
; buff_cnt --> number of characters currently in buffer
; buff_size --> size of buffer, also is address of last character
; in buffer
; insert_ptr --> pointer to last character placed into buffer
; data_seg --> data segment of buffer data
;
; exit: insert_ptr --> pointer to character just inserted into buffer
; buff_cnt --> updated number of characters in buffer
;
;-----------------------------------------------------------------------------
insert proc near
;-----------------------------------------------------------------------------
; the following code needs to be checked to see if it is necessary (probably
;-----------------------------------------------------------------------------
cmp pointer_set,0 ;it timer interrupt modifyed yet
jnz insert1 ;continue if so
push es ;save current extra segment
mov bx,0 ;set the segment address to zero
mov es,bx ;do it
mov bx,20h ;address of int vector 08
mov word ptr es:[bx],offset prtout ;set the print out address
mov es:[bx+2],cs ;set the segment
pop es ;restore our previos extra segment
mov pointer_set,0ffh ;set the pointer flag
insert1:
mov bx,buff_cnt ;get the current buffer count
cmp buf_size,bx ;check for buffer full
jz insert ;loop untill space is available
push ds ;save data segment
push ax ;save the character onto the stack
inc insert_ptr ;bump insert pointer one position
mov bx,buf_size ;get the last position in the buffer
cmp insert_ptr,bx ;are they the same
jbe insert2 ;continue if not
mov insert_ptr,0 ;reset the pointer to begging of buffer
insert2:mov si,insert_ptr ;get the current insert pointer
mov ds,data_seg ;get the data segment of our buffer
pop ax ;restore our character from the stack
cli ;stop interrupts
mov [si],al ;put it into memory
pop ds ;restore our local data segment register
inc buff_cnt ;increment count of characters in buffer
sti ;restart interrupts
ret
insert endp
;-----------------------------------------------------------------------------
; flush buffer request routine
;
; this procedure flushes the buffer by calling a procedure called flush.
; it then jmps to exit to set the status word to done and exits.
;-----------------------------------------------------------------------------
out_flush proc near
call flush ;go flush contents of the memory buffer
jmp exit ;set status word to done and exit
out_flush endp
;-----------------------------------------------------------------------------
; flush buffer routine
;
; this is the procedure which actually performs the clearing of the buffer.
; interrupts are disabled during this action. pull_ptr, insert_ptr, buff_cnt
; are all zeroed. this sets the amount of characters in the buffer to zero,
; front of the buffer.
;
; entry: pull_ptr --> pointer to next character to send to printer
; insert_ptr --> pointer to last character inserted into buffer
; buff_cnt --> number of characters currently in buffer
;
; exit: pull_ptr, insert_ptr, buff_cnt --> all reset to zero (reset)
;-----------------------------------------------------------------------------
flush proc near
cli ;turn off interrupts while we work
mov ax,0
mov pull_ptr,ax ;zero out the pull
mov insert_ptr,ax ;and insert pointers
mov buff_cnt,ax ;reset amount of data avail
sti ;restart interrupts
ret
flush endp
;-----------------------------------------------------------------------------
; buffer status routine entry point
;
; this is the interrupt procedure which is vectored to by ioctl
; which was set up in init. the buffer status program is used
; to perform io control functions of: flushing the buffer, getting and setting
; the port number, getting the buffer size, amount of characters in the buffer,
; and getting and setting the processing priority (background or foreground).
; since this status procedure is interrupt driven, it must save all registers,
; perform the desired operation, and return via an iret (interrupt return).
; the ax register, on entry, contains the request number. it is doubled and
; used as an offset into a table to determine the address of the servicing
; procedure. on exit from the servicing procedure, bx contains the requested
; information.
;
; entry: ax --> status request command number
;
; exit: bx --> return value from status request servicing procedure
; (buffer count, port number, etc.)
;-----------------------------------------------------------------------------
ioctl_buf struc
ioctl_ifunct dw ? ; the calling function
ioctl_resp dw ? ; any response from the routine
ioctl_buf ends
ioctl_in:
ioctl_out:
mov ax,es:[di.ioctl_ifunct] ; get the function
mov bx,es:[di.ioctl_resp] ; get extended function
cmp ax,10 ;test the request
jb status1 ;continue if valid
mov ax,1 ;change it to a number one request
status1:add ax,ax
mov si,offset table ;point to start of table
xchg bx,ax ;put in bx
mov si,[bx+si] ;get routine address out of table
xchg bx,ax ;swap back around
call si ;call the requested routine
mov es:[di.ioctl_resp],bx ; put the results back
mov al,0 ; no errors
jmp exit
;-----------------------------------------------------------------------------
; special action table
;
; this is the table of procedures to service the status requests from
; ioctl calls
;-----------------------------------------------------------------------------
table dw flush ;flush buffer
dw get_port ;go get the printer port number
dw set_port ;reassign printer port
dw get_buf_siz ;go get printer buffer size
dw get_count ;go get count of characters in buffer
dw set_priority ;set current processing priority
dw get_priority ;get current processing priority
dw ident ;return identity code to verify us
dw pause_prn ;pause the printer if a 1
dw reprint_page ; move buffer pointer back to start of
; page
;-----------------------------------------------------------------------------
; reprint current page
;
; This procedure will search bacwards through the buffer looking
; for a form feed character. This makes the assupmtion the user wishes to
; reprint the page he is on. It will make a saftey check to see buffer does
; not overflow. If no form feed found,it will just return with no pointer
; change
reprint_page proc near
mov si,pull_ptr ; get current offset
push ds
mov ds,data_seg ; buffer segment
back_scan_loop:
cmp byte ptr[si],formfeed ; is it what we want?
je page_restart
dec si
jz overflow_test
jmp back_scan_loop
overflow_test: ; check for character only here
cmp byte ptr[si],formfeed
je page_restartl
pop ds
; no form feed was found, just restore ds and skip out of here!
no_page:
xor bx,bx ; nothing to report back
ret
page_restart:
; update pointers
dec si ; point to form feed
page_restartl:
pop ds
mov pull_ptr,si
jmp short no_page
reprint_page endp
;-----------------------------------------------------------------------------
;-----------------------------------------------------------------------------
; get current port number
;
; this procedure returns the current port number in the bl register as an
; ascii digit 1-4 (31h-34h).
;
; entry: port_number --> current port number the buffer is assigned to
;
; exit: bl --> ascii digit of the current buffer port number
; bh := port type. 0 com, 1 parallel
;-----------------------------------------------------------------------------
get_port proc near
xor bx,bx ;clear out bx
mov bl,port_number ;get the printer port in use
mov bh,[port_type]
ret
get_port endp
;-----------------------------------------------------------------------------
; get current buffer size
;
; this procedure returns the current buffer size (capacity) in the bx
; register. it is in the range of 0 to 65535.
;
; entry: buf_size --> assigned capacity of the buffer
;
; exit: bx --> assigned capacity of the buffer (0 - 65535)
;-----------------------------------------------------------------------------
get_buf_siz proc near
mov bx,buf_size ;load value of our buffer size
ret
get_buf_siz endp
;-----------------------------------------------------------------------------
; identity
;
; this procedure just returns a 16 bit id code saying we are
; spooler interrupt.
;
;-----------------------------------------------------------------------------
ident proc near
mov bx,55aah ; a checkerboard
ret
ident endp
;-----------------------------------------------------------------------------
; reassign port routine
;
; this procedure sets the bufferred port number to the value received in
; the bl register from the int 65h.
;
; entry: bl --> new port number for bufferring (0,1) if com (0,1,2) if parallel
; bh = port type. 0 com, 1 for parallel
;
; exit: port_number --> updated to new port number
;-----------------------------------------------------------------------------
set_port proc near
mov port_number,bl ;save the new port number
mov [port_type],bh
ret
set_port endp
;-----------------------------------------------------------------------------
; get count of characters in printer buffer
;
; this procedure returns the amount of characters currently in the buffer
; waiting for output to the designated port.
;
; entry: buff_cnt --> current amount of characters in buffer
;
; exit: bx --> current amount of characters in buffer returned
;-----------------------------------------------------------------------------
get_count proc near
mov bx,buff_cnt ;get amount of data in memory buffer
ret
get_count endp
;-----------------------------------------------------------------------------
; set processing priority
;
; this procedure sets the processing priority. the priority dictates
; how the character-output-to-the-port procedure services the output. the
; priority is the maximum number of times the output procedure will loop
; waiting for the port to become ready (not busy). a low priority will only
;
; entry: bx --> new priority number
;
; exit: priority --> updated priority number for use by the buffer
;-----------------------------------------------------------------------------
set_priority proc near
mov priority,bx ;save the new priority
ret
set_priority endp
;-----------------------------------------------------------------------------
; get processing priority
;
; this procedure returns the current processing priority in the bx
; register.
;
; entry: priority --> current processing priority
;
; exit: bx --> returned processing priority
;-----------------------------------------------------------------------------
get_priority proc near
mov bx,priority ;get the current processing priority
ret
get_priority endp
;-----------------------------------------------------------------------------
; handle pause control of printer output
;
; This procedure will set pause on printer output,or turn it off.
; Also returns status of pause switch in bl
;
; (BX) entry: 0 -------> Do nothing, just set status
; 1 -------> Turn on pause
; 2 -------> Turn off pause (print)
;
; (BL) exit: 0 -------> Printer running
; (BL) -1 -------> Printer is paused
;-----------------------------------------------------------------------------
pause_prn proc near
cmp bx,0
je pstat_ret
cmp bx,2
ja pstat_ret
je off_pause
on_pause:
mov byte ptr ppause,-1
jmp short pstat_ret
off_pause:
mov byte ptr ppause,0
pstat_ret:
mov bl,byte ptr ppause
xor bh,bh
ret
pause_prn endp
;-----------------------------------------------------------------------------
; parallel interrupt intercept routine
;
; this procedure is set-up as the new parallel printer interrupt routine.
; when an interrupt occurs, control is diverted to this routine. a check is
; performed to see if the port being output to is the port we have set-up a
; buffer for. if it is not, then the regular, old ibm bios routine is called.
; we re-vectored the old ibm bios routine to int 67h (pretty slick, huh?).
; then a test is done to see if the desired action is to output a character,
; initialize the port, or get the status of the port.
; procedure.
; if the request is for a port status, our procedure checks to see if the
; buffer is full, if it is full, we return busy and selected in the ah status
; register. if the buffer is not full, we return not busy and selected.
; if the request is to print a character in al, all registers are saved,
; the insert procedure is called to insert the character in the buffer, and
; a status check is performed for return from the interrupt.
;
; entry: ah --> interrupt request type (0,1,2)
; al --> character to output
; dx --> port number to work with (status, output, etc)
; port_number --> the currently bufferred output port
; buff_cnt --> current number of characters in the buffer
; buf_size --> current capacity of the buffer
;
; exit: ah --> port status returned
;-----------------------------------------------------------------------------
par_incep proc near
sti ;restart interrupts
cmp cs:[port_type],1 ; parallel=1, com=0
jnz par_incep9
cmp dl,cs:port_number ;is it the port we are doing spooling for
jnz par_incep9 ;transfer control to rom bios if not
cmp ah,1 ;is it a reset request
jz par_incep1 ;wait for buffer empty and reset
cmp ah,2 ;is it a status request
jz par_incep2 ;make status determination
call insert_a_char
par_incep2:
push ax ;save inital register onto the stack
mov ax,cs:buff_cnt ;get current buffer count
cmp ax,cs:buf_size ;is buffer full ?
pop ax ;restore al from stack
jz par_incep3 ;indicate buzy *** what about the rest of the status like out of paper
mov ah,10h ;indicate selected
iret
par_incep3:
mov ah,10h ;indicate selected and buzy
iret
par_incep1:
cmp cs:buff_cnt,0 ;is buffer empty
jnz par_incep1 ;loop untill it is
par_incep9:
int 67h ;hand control over to the rom bios
iret ;return to calling routine
par_incep endp
;--------------------------------------------------------------------
com_incep proc
; this routine will replace the ibm int 14h for rs232 communication.
sti
cmp cs:[port_type], 0 ; skip this routine if flash prn is using parallel
jnz com_incep9
cmp cs:[port_number], dl ; skip this routine if flash prn is using different com ports
jnz com_incep9
cmp ah, 0 ; skip if they want to set baud rate, etc
jz com_incep9
cmp ah, 1 ; insert a char in the buffer
jz com_incep1
cmp ah, 2 ; get a char (set error bits and return)
jz com_incep2
cmp ah, 3 ; status
jz com_incep9
iret
com_incep1:
call insert_a_char
push dx
call get_port_address
call get_com_status
pop dx
push ax
mov ax,cs:buff_cnt ;if the buffer is full set the high bit of ah
cmp ax,cs:buf_size
pop ax
jnz c1
or ah, 80h
c1:
iret
com_incep9:
int 66h
iret
com_incep2: ; set all the error bits
mov ah, 1001111b
iret
com_incep endp
;--------------------------------------------------------------------
insert_a_char proc
push ax
push bx
push si
push ds
;-----------------------------------------------------------------------------
; establish local addressing
; this is an important section because it sets-up the correct data
; segment for the buffer prior to calling insert to place the character in al
; into the buffer.
;-----------------------------------------------------------------------------
push cs
pop ds
call insert ;insert the character into the printer buffer
pop ds
pop si ;restore saved registers
pop bx ;from the stack
pop ax
ret
insert_a_char endp
;-----------------------------------------------------------------------------
; dummy farjump procedure
; this procedure is initially a do-nothing procedure. but, after init
; gets done with it, it is replaced by the ibm rom bios timer interrupt routine.
; (check out the jmp farjmp instruction at the label prtout9:). the farjmp
; label is replaced by init with the address of the timer interrupt routine.
; that way we can output a character from the buffer to the printer port and
; then service the timer interrupt in the normal fashion using the same ibm
; bios routine (another slick move!!!).
;-----------------------------------------------------------------------------
; farjmp proc far
; ret
; farjmp endp
;-----------------------------------------------------------------------------
; printer output routine
;
; this is the procedure that replaces the standard timer interrupt. that
; way whenever the timer is interrupted we can try to get a character out of
; the buffer to the output port. a neato trick is that the standard timer
; interrupt code is jmped to at the very end of this code. this way the
; standard code is executed after ours (no applause, please!).
; an important item to take note of is the fact that the data segment is
; restored from the code segment prior to calling chrout. the code segment
; stays the same throughout the driver.
;-----------------------------------------------------------------------------
prtout proc near
sti ;restart interrupts for other activitys
push ax ;save the registers we will use
push bx
push dx
push si
push ds
push es
push cs
pop ds
call chrout ;do character out processing
pop es
pop ds
pop si
pop dx
pop bx
pop ax
prtout9:db 0eah,0,0,0,0 ;far jump to old timer interrupt routine
prtout endp
;-----------------------------------------------------------------------------
; printer port character output routine
;
; this procedure handles removing a character from the buffer and
; outputting it to the designated port. alot of activities happens in this
; routine: buffer manipulation, status checking on the desired port and finally
; outputting the character to the data port.
; the time-out counter (loop_cnt) is initialized to the processing priority.
; really it is a counter that controls how many times to loop until the
chrout proc near
cmp byte ptr ppause,-1 ; are we paused ?
jz chrout9 ; then skip it for now!
mov ax,priority ;get current priority count
mov loop_cnt,ax ;set number of times to loop
chrout1:
cmp buff_cnt,0 ;is the buffer empty
jz chrout9 ;exit if so
call get_port_address
call busytest
jc chrout7
inc pull_ptr ;bump the pull pointer one chr
mov bx,buf_size ;get max buffer size
cmp pull_ptr,bx ;test for overflow
jbe chrout2 ;continue if no problem
mov pull_ptr,0h ;reset pointer to begining of buffer
chrout2:
mov si,pull_ptr ;get current pull pointer
mov es,data_seg ;get segment value of the data buffer
cli ;turn off interrupts
mov al,es:[si] ;get character out of the buffer
mov ah, al
dec buff_cnt ;adjust buffer count
call outputal
sti
cmp ah,1bh ;was it some kind of control character
jb chrout9 ;exit as there should be a delay comming
chrout8:dec loop_cnt ;addjust the loop count
jnz chrout1 ;loop if not done
chrout9:ret
chrout7:mov ax,priority ;get current priority
cmp loop_cnt,ax ;has it ever been ready
jnz chrout8 ;continue if so
ret
chrout endp
;--------------------------------------------------------------------
get_port_address proc
; call: [port_type] = 0 com, 1 if parallel
; [port_number] = 0, 1, 2
; return: dx = port address
push ax
push es
push si
mov ax,0040h ;set extra segment to look
mov es,ax ;into the rombios data area
mov si,8 ;load offset to par. printer table
cmp cs:[port_type], 0
jnz g1
mov si, 0
g1:
mov al,cs:[port_number] ;get the current port number
cbw ;make it a 16 bit value
add si,ax ;do power of two
add si,ax ;to compute displacement into address table
mov dx,es:[si] ;get par. port address out of the table
pop si
pop es
pop ax
ret
get_port_address endp
;--------------------------------------------------------------------
busytest proc
; call: dx = port address
; [port_type] = 0 com, 1 par
; return: carry is set if a char. con not be output (busy).
push dx
cmp [port_type], 1
jnz com_test
inc dx ; parallel busy test
in al,dx
test al,80h
jz busy_exit
jmp not_busy_exit
com_test:
add dx, 6 ; com busy test
in al, dx
test al, 20h
jz busy_exit
test al, 10h
jz busy_exit
dec dx
in al, dx
test al, 20h
jz busy_exit
jmp not_busy_exit
busy_exit:
pop dx
stc
ret
not_busy_exit:
pop dx
clc
ret
busytest endp
;--------------------------------------------------------------------
outputal proc
; output a character to the com or par. ports. assume the port is not busy.
; call: dx = port address
; [port_type] = 0 com, 1 par
; al = character to output
cmp [port_type], 1
jnz com_output
out dx, al ; parallel output (see ibm rom bios)
inc dx
mov al, 0dh
inc dx
out dx, al
mov al, 0ch
out dx, al
ret
com_output:
push ax ; com output (see ibm rom bios)
add dx, 4
mov al, 3
out dx, al
sub dx, 4
pop ax
out dx, al
ret
outputal endp
;--------------------------------------------------------------------
get_com_status proc
; see ibm rom bios page a-23
; call: dx = port address of com
; return: ah = line status
; al = modem status
add dx, 5 ; point to the control port
in al, dx ; line control status
mov ah, al
inc dx
in al, dx ; modem status
ret
get_com_status endp
;--------------------------------------------------------------------
db 16 dup(?)
;
; init routine
;
init proc near
cld ;clear direction
lds si,rh_seg ;get pointer to request header
lds si,18[si] ;get pointer to config message
init1: mov bx,1 ;start with a value of one k
lodsb ;get character
cmp al,0dh ;is it a return
jz init3 ;exit determination if so
cmp al,2fh ;is it a slash seperating values
jz init2 ;if so get value
cmp al,2dh ;is it a dash character
jnz init1 ;loop if no determination
init2: lodsb ;get high order character
sub al,30h ;convert to binary
jb init3 ;exit determination if not a digit
cmp al,0ah ;is if greater then the number 9
jnb init3 ;exit if so
mov bl,al ;put value in bl
cmp byte ptr[si],30h ;check next character to see if an digit
jb init3 ;not a digit go onto next test
lodsb ;get the digit
sub al,30h ;convert to binary
jb init3
cmp al,0ah ;check for greater then 9
jnb init3 ;go onto next test if not
xchg bx,ax ;multiply orginal value by 10
mov cl,0ah ;value to multiply by
mul cl ;do it
add al,bl ;add in new digit
xchg bx,ax ;place in cx register
init3: cmp bx,63 ;is it greater then 64 k
jbe init4 ;continue if so
mov bx,63 ;fource to to 64k max
init4: mov ax,1024 ;value for one k
mul bx ;compute total number of k
cmp dx,+01 ;check for 16 bit over flow
jb init5
mov ax,0ffffh ;make a mask for 64 k
init5: mov cs:buf_size,ax ;save size of buffer
;
; now check for printer port to use
;
init5a: lodsb ;get next character in the string
cmp al,0dh ;is it the end of line
jz init7 ;exit determination if so
cmp al,2fh ;is it a slash character that seperates values
jz init6 ;continue if so
cmp al,2dh ;is it a dash that can seperate it to
jnz init5a ;ignore if not
init6: lodsb ;get next character
and al,0dfh ;make it a upper case character
cmp al,'C' ;is it the letter "c" for com port
jnz init10 ;if not "c" then test for "l"
mov cs:[port_type],0 ;set port_type to com (value of 0)
jmp init11 ;now go get port number
init10: cmp al,'L' ;is it the letter "l" for lpt port
jnz init7 ;exit if not a "l" or "c"
mov cs:[port_type],1 ;set port_type to lpt (value of 1)
init11:
lodsb ;get next character, which should be the port number
sub al,31h ;convert to binary number
jb init7 ;exit if less then the digit "1"
cmp al,03 ;make sure not greater then "4"
jnb init7 ;bypass if error
call get_port_address ; make sure the port is ready there
cmp dx, 0
jz init7
; cbw ;make 16 bit value
; push ax ;save the port number onto the stack
; add ax,ax ;double it for table lookup
; mov bx,ax ;put the table offset value into bx
; push es ;save our segment register
; mov ax,0040h ;set our segment value to rom bios area
; mov es,ax ;do it
; mov di,0008*port_type ;displacement into the bios area
; cmp es:word ptr[bx+di],0 ;make sure the port really is there
; pop es ;restore our previos data segment
; pop ax ;restore port number from the stack
; jz init7 ;use standard port value if not
mov cs:port_number,al ;save the port number for future use
jmp init8
init7: mov cs:[port_type],1 ; lpt
mov cs:port_number,0 ;fource port number to lpt1:
init8: mov ax,cs ;get value of current code segment
mov ds,ax ;set ds to point at code segment
;
; get current interrupt vector for timer interrupt
;
push es ;save the segment register
mov ax,3508h ;vector number for irq0
int 21h ;get the vector
mov word ptr prtout9+1,bx ;save the offset
mov word ptr prtout9+3,es ;save the segment it will belong in
pop es ;restore the extra segment register
;
; setup interrupt vector 08h (timer) to print output routine
;
; mov ax,2508h ;dos request
; mov dx,offset prtout ;pointer to our routine
; int 21h
;
; get pointer to current parallel printer routine
;
push ds ;save our data segment onto the stack
mov ax,3517h ;dos request
int 21h
;
; transfer it to int 67h vector for use by programs that want to
; use additional printers
;
push es ;save the segment address onto stack
pop ds ;return it in data segment register
mov dx,bx ;move offset to dx register
mov ah,25
mov al,user_int ;dos request to init 67h (default)
int 21h
pop ds ;restore our local data segment
;
; setup code to point parallel printer intercept routine
;
mov ax,2517h ;dos request
mov dx,offset par_incep ;pointer to our routine
int 21h
push ds
mov ah, 35h ; get rs232_io vector and reassign it to vector 66h
mov al, 14h
int 21h ; es:bx = vector
push es
pop ds
mov dx, bx
mov ah, 25h
mov al, 66h
int 21h
pop ds
mov ah, 25h ; assign our com_incep routine to the old rs232_io int 14h
mov al, 14h
mov dx, offset com_incep
int 21h
;
; compute starting segment for the data buffer
;
mov bx,offset init ;point to the start of our init routine
mov al,0fh ;value to compute segment address
and al,bl ;mask off bottom four bits
jz init9 ;allready on segment boundry
add bl,10h ;bump lenght on one segment
init9: mov dx,bx ;put value into dx
mov cl,04 ;amount to shift right
shr dx,cl ;do it
mov ax,cs ;get current code segment
add ax,dx ;add to our segment length
mov data_seg,ax ;save that as the start of our printer buffer
mov ax,buf_size ;get the current buffer size
add ax,bx ;add it to the code lenght
mov [ending_address], ax
lds si,rh_seg ;fill in the request header the point
mov [si+0eh],ax ;past our useage
mov [si+10h],cs
jmp exit ;set status word to done and exit
init endp
cseg ends
end